GridByIniFloat Subroutine

private subroutine GridByIniFloat(ini, grid, section, time)

read a grid_real using information stored in ini configuration file

Arguments

Type IntentOptional Attributes Name
type(IniList), intent(in) :: ini
type(grid_real), intent(out) :: grid
character(len=*), intent(in) :: section
type(DateTime), intent(in), optional :: time

Variables

Type Visibility Attributes Name Initial
real(kind=float), public :: centralMeridian
integer, public :: epsg
character(len=300), public :: file
character(len=100), public :: fileFormat
type(DateTime), public :: gridTime

time of the grid to read

integer, public :: i
integer, public :: j
real(kind=float), public :: offset
real(kind=float), public :: scale_factor
character(len=100), public :: stdName

standard name of the variable to read

integer(kind=short), public :: timeSync
real(kind=float), public :: valid_max
real(kind=float), public :: valid_min
character(len=100), public :: variable

variable to read


Source Code

SUBROUTINE GridByIniFloat &
!
(ini, grid, section, time) 

USE Inilib, ONLY: &
!Imported type definitions:
IniList, &
!imported routines:
IniReadString, IniReadReal, KeyIsPresent, IniReadReal, IniReadInt

USE StringManipulation, ONLY: &
!Imported routines:
StringToUpper, StringToLower, StringToShort

USE Chronos, ONLY: &
!Imported type definitions:
DateTime, &
!Imported operands:
ASSIGNMENT( = )

USE GeoLib , ONLY: &
  !Imported routines:
  DecodeEPSG
!SetCRS, ScanDatum, &
!SetGeodeticParameters, SetTransverseMercatorParameters, &
!SetSwissParameters, &
!Imported parameters:
!GEODETIC, TM, SOC, &
!EAST, WEST, NORTH, SOUTH, ROME40

USE Units, ONLY: &
!Imported parameters:
degToRad


IMPLICIT NONE

!arguments with intent in:
TYPE (IniList), INTENT(IN) :: ini
CHARACTER (LEN = *), INTENT (IN) :: section
TYPE (DateTime), OPTIONAL, INTENT (IN) :: time

!arguments with intent out:
TYPE (grid_real), INTENT (OUT) :: grid

!local variables:
CHARACTER (LEN = 100) :: fileFormat
CHARACTER (LEN = 300) :: file
CHARACTER (LEN = 100) :: variable  !!variable  to read
CHARACTER (LEN = 100) :: stdName  !!standard name of the variable  to read
!CHARACTER (LEN = 100) :: grid_mapping
INTEGER               :: epsg
INTEGER ( KIND = short) :: timeSync
!CHARACTER (LEN = 100) :: datum
TYPE (DateTime)       :: gridTime  !!time of the grid to read
REAL (KIND = float)   :: scale_factor
REAL (KIND = float)   :: offset
REAL (KIND = float)   :: valid_min
REAL (KIND = float)   :: valid_max
REAL (KIND = float)   :: centralMeridian
!INTEGER               :: grid_datum
!INTEGER (KIND = short) :: utm_zone
INTEGER :: i,j

!-----------------------------end of declaration-------------------------------

  file = IniReadString ('file', ini, section)
  
  IF (KeyIsPresent ('format', ini, section)) THEN
    fileFormat = StringToUpper ( IniReadString ('format', ini, section) )
  ELSE
    CALL Catch ('error', 'GridOperations',  &
    'format not specified for grid: ',  &
     argument = section )
  END IF
  
  !read grid
  IF ( fileFormat == 'ESRI-ASCII' ) THEN
    CALL NewGrid (grid, file, ESRI_ASCII)
  ELSE IF (fileFormat == 'ESRI-BINARY' ) THEN
    CALL NewGrid (grid, file, ESRI_BINARY)
  ELSE IF ( fileFormat == 'NET-CDF' ) THEN
    IF (KeyIsPresent('variable', ini, section)) THEN
      variable = IniReadString ('variable', ini, section) 
      IF (KeyIsPresent('time', ini, section)) THEN
        gridTime = IniReadString ('time', ini, section)
        CALL NewGrid (grid, file, NET_CDF, variable = variable, time = gridTime)
      ELSE IF (KeyIsPresent('sync-initial-time', ini, section)) THEN
          timeSync = IniReadInt ('sync-initial-time', ini, section)
          IF ( timeSync == 1) THEN
              CALL SyncTime ( file, time, gridTime )
              CALL NewGrid (grid, file, NET_CDF, variable = variable, time = gridTime)
          END IF
      ELSE
        CALL NewGrid (grid, file, NET_CDF, variable = variable)
      END IF
    ELSE IF (KeyIsPresent('standard_name', ini, section)) THEN
      stdName = IniReadString ('standard_name', ini, section) 
      IF (KeyIsPresent('time', ini, section)) THEN
        gridTime = IniReadString ('time', ini, section)
        CALL NewGrid (grid, file, NET_CDF, stdName = stdName, time = gridtime)
      ELSE
        CALL NewGrid (grid, file, NET_CDF, stdName = stdName)
      END IF
    ELSE
        CALL Catch ('error', 'GridOperations',  &
              'variable or standard name not defined while reading netcdf: ',  &
               argument = section )
    END IF
  ELSE
    CALL Catch ('error', 'GridOperations',  &
                'format not supported: ',  &
                argument = fileFormat )
  END IF
  
  !apply scale factor if given
  IF (KeyIsPresent ('scale_factor', ini, section) ) THEN
    scale_factor = IniReadReal ('scale_factor', ini, section)
    DO i = 1, grid % idim
      DO j = 1, grid % jdim 
        IF ( grid % mat (i,j) /= grid % nodata ) THEN   
          grid % mat (i,j) = grid % mat (i,j) * scale_factor
        END IF
      END DO
    END DO   
  END IF
  
  !add offset if given
  IF (KeyIsPresent ('offset', ini, section) ) THEN
    offset = IniReadReal ('offset', ini, section)
    DO i = 1, grid % idim
      DO j = 1, grid % jdim 
        IF ( grid % mat (i,j) /= grid % nodata ) THEN   
          grid % mat (i,j) = grid % mat (i,j) + offset
        END IF
      END DO
    END DO     
  END IF

  !check upper bound if given
  IF (KeyIsPresent ('valid_max', ini, section) ) THEN
    valid_max = IniReadInt ('valid_max', ini, section)
    DO i = 1, grid % idim
      DO j = 1, grid % jdim 
        IF ( grid % mat (i,j) /= grid % nodata ) THEN
          IF (grid % mat (i,j) > valid_max ) THEN   
            grid % mat (i,j) = valid_max
          END IF
        END IF
      END DO
    END DO     
  END IF

  !check lower bound if given
  IF (KeyIsPresent ('valid_min', ini, section) ) THEN
    valid_min = IniReadInt ('valid_min', ini, section)
    DO i = 1, grid % idim
      DO j = 1, grid % jdim 
        IF ( grid % mat (i,j) /= grid % nodata ) THEN
          IF (grid % mat (i,j) < valid_min ) THEN   
            grid % mat (i,j) = valid_min
          END IF
        END IF
      END DO
    END DO     
  END IF
  
  !read coordinate reference system if given
  IF (KeyIsPresent ('epsg', ini, section) ) THEN
     epsg = IniReadInt ('epsg', ini, section)
     grid % grid_mapping = DecodeEPSG (epsg)
  ELSE
    CALL Catch ('error', 'GridOperations',  &
      'epsg not specified for grid: ',  &
     argument = section ) 
  END IF
  
  !IF (KeyIsPresent ('grid_mapping', ini, section) ) THEN
  !   grid_mapping = IniReadString ('grid_mapping', ini, section)
  !   IF (KeyIsPresent ('datum', ini, section) ) THEN
  !     datum = IniReadString ('datum', ini, section)
  !   ELSE
  !     datum = 'WGS84'
  !   END IF
  !   grid_datum = ScanDatum (datum)
  !   !set reference system
  !   IF (StringToUpper(grid_mapping) == 'GEODETIC') THEN
  !     CALL SetCRS (GEODETIC, grid_datum, grid % grid_mapping)
  !     !default prime_meridian = 0.
  !     CALL SetGeodeticParameters (grid % grid_mapping, prime_meridian = 0.0)
  !   ELSE IF (StringToUpper(grid_mapping(1:11)) == 'GAUSS-BOAGA') THEN
  !     !gauss boaga is a particular case of transverse-mercator
  !     CALL SetCRS (TM, ROME40, grid % grid_mapping)
  !     IF (StringToUpper(grid_mapping(13:16)) == 'EAST') THEN
  !       CALL SetTransverseMercatorParameters &
  !           (grid % grid_mapping, lat0 = 0., centM = 15. * degToRad, &
  !            falseE = 2520000., falseN = 0., k = 0.9996)
  !     ELSE 
  !       CALL SetTransverseMercatorParameters &
  !           (grid % grid_mapping, lat0 = 0., centM = 9. * degToRad, &
  !            falseE = 1500000., falseN = 0., k = 0.9996)
  !     END IF
  !   ELSE IF (StringToUpper(grid_mapping(1:3)) == 'UTM') THEN
  !       !UTM is a particular case of transverse-mercator
  !       CALL SetCRS (TM, grid_datum, grid % grid_mapping)
  !       utm_zone = StringToShort(grid_mapping(4:5))
  !       IF ( utm_zone >= 31) THEN
  !          centralMeridian = (6 * utm_zone - 183) * degToRad
  !       ELSE
  !          centralMeridian = (6 * utm_zone + 177) * degToRad
  !       END IF
  !       IF (StringToUpper(grid_mapping(6:6)) == 'N' ) THEN
  !         CALL SetTransverseMercatorParameters &
  !           (grid % grid_mapping, lat0 = 0., centM = centralMeridian, &
  !            falseE = 500000., falseN = 0., k = 0.9996)
  !       ELSE
  !         CALL SetTransverseMercatorParameters &
  !           (grid % grid_mapping, lat0 = 0., centM = centralMeridian, &
  !            falseE = 500000., falseN = 10000000., k = 0.9996)
  !       END IF
  !       
  !    ELSE IF (StringToUpper(grid_mapping(1:5)) == 'SWISS') THEN
  !       CALL SetCRS (SOC, grid_datum, grid % grid_mapping)
  !       CALL SetSwissParameters &
  !           (grid % grid_mapping, latc = 0.819474, lonc = 0.129845, &
  !            azimuth = 1.570796, falseE = 600000., falseN = 200000., k = 1.)
  !   END IF
  !
  !END IF
  
  !varying mode
   IF (KeyIsPresent ('varying_mode', ini, section) ) THEN
   
     grid % varying_mode = StringToLower(IniReadString ('varying_mode', ini, section))
     
     !check option is valid
     IF (grid % varying_mode (1:8) /= 'sequence' .AND. &
         grid % varying_mode (1:6) /= 'linear' ) THEN
         
          CALL Catch ('error', 'GridOperations',  &
           'invalid varying_mode option for grid: ',  &
           code = unknownOption, argument = section )
      
     END IF    
         
   ELSE !default to 'sequence'
   
     grid % varying_mode = 'sequence'
   
   END IF
  
END SUBROUTINE GridByIniFloat